λ-Types on the λ-Calculus with Abbreviations

نویسنده

  • FERRUCCIO GUIDI
چکیده

ions over incomplete types (i.e. types that do not specify the functional structure of their inhabitants completely) are meant to simulate the Π-abstractions of the λ-cube [Barendregt 1993] and the author sees fitting the Π binder into λδ architecture as a very challenging task. In particular it would be interesting to relate this extension of λδ to COC since this calculus has been fully specified in coq [Barras 1996] as well as λδ itself, and the author sees the possibility of certifying rigorously the mappings that may exist between these systems. The novelty of λδ extended with Π would be that Π could appear at the level of terms and inside contexts rather than only at the level of types. In the perspective of relating this extension with a CIC with universes, we would also need a mechanism that makes Sorth a sub-sort of Sortk when h < k. Finally we would like to mention that the conditioned version of the exclusion binder, which we denote with χvx (block 1), can be considered as well but at the moment we are not clear about its applications. A. JUSTIFYING THE STRUCTURAL FRAGMENT OF MTT WITH λδ In the present appendix we show how the structural rules of the Minimal Type Theory (MTT) [Maietti and Sambin 2005] can be justified trough the rules of λδ and we proceed in three steps. In Appendix A.1 we show that λδ can be used as a theory of expressions for MTT. In Appendix A.2 we show that λδ type assignment and conversion can model MTT judgements. In Appendix A.3 we show that λδ rules can model MTT structural rules. In order to achieve this objective, we propose to remove η-conversion and the so-called Cont judgement from MTT, and to perform 4Describing the computational model of a Whole Adaptive System in terms of typed λ-calculus requires much more than conditioned abbreviations: in particular we feel that anti-binders, in the sense of [Hendriks and van Oostrom 2003], might play an important role for this task. ACM Transactions on Computational Logic, Vol. V, No. N, Month 20YY. λ-Types on the λ-Calculus with Abbreviations · 25 some changes to the MTT rules called var and prop-into-set. Our justification is based on a straight forward mapping of judgements involving types built by dependent abstraction. The underlying idea is to map the inhabitation judgements to the type judgement ⊢ : (at different levels of the type hierarchy) and the equality judgements to the conversion judgement ⊢ ⇔. When referring to MTT we will use the notation of [Maietti and Sambin 2005]. A.1 λδ can serve as a Theory of Expressions for MTT According to [Maietti and Sambin 2005] the theory of expressions underlying MTT is the one, originally due to Martin-Löf, underlying CTT [Nordström et al. 1990] without combinations and selections. Moreover typed abstractions (á la Church) are used in place of untyped ones. Therefore MTT-expressions are based on variables, primitive constants, defined constants, applications and typed abstractions. Moreover every meaningful MTT-expression has an arity, which is a type expression of the instance of λ→ with one type constant 0. Equality between MTT-expressions is defined up to definitional equality: a rewriting mechanism that incorporates αβη-conversion, and δ-conversion (equality between the definiendum and the definiens of an abbreviation). In our proposal we leave η-conversion aside because we suspect that this conversion is not strictly necessary in MTT and is used just as syntactic sugar. In any case η-conversion is available for λ-abstractions as expected (see Theorem 1(8)). As a matter of fact λδ can handle the mentioned ingredients as follows. Variables, defined constants, applications and typed abstractions are term constructions of the calculus (see Definition 2). In particular we regard all definitions as δ-items of a global context Cy in which we close every term. Primitive constants are regarded as references to λ-items (i.e. declarations) that are also part of the context Cy. So Cy contains declarations and definitions. Types can be substituted for arities. Notice that arities exist in λδ as well (see Definition 15) and that typed terms have an arity (see Theorem 9(3)). Finally definitional equality is handled through context-dependent parallel conversion (see Definition 9) that incorporates αβδ-conversion. A.2 λδ Judgements can express MTT Judgements MTT features six main judgements that fall into two classes: declarations and equalities. Declarations state that an expression is a legal proposition, a legal data type, or a legal element of a data type. Equalities state that two legal propositions, data types, or elements of a data type are semantically equal. Parametric expressions are allowed and each main judgement includes an explicit context where the local parameters are declared. Other parameters, shared among all judgements of a given rule, are declared in an implicit context extracted from the premises of that rule. Summing up, a legal MTT-expression requires three contexts: the explicit context (provided by the judgement containing that expression), the implicit context (extracted from the premises of the rule containing that judgement) and the global context (for global declarations and abbreviations). A judgement stating that an explicit context is legal, is also provided. ACM Transactions on Computational Logic, Vol. V, No. N, Month 20YY. 26 · Ferruccio Guidi We can map these judgements to λδ-judgements in the way we explain below. Sort hierarchy. We need two sorts Prop and Set that we regard as aliases of Sort0 and Sort1 respectively (we can include these abbreviations in the global context Cy). We also set the sort hierarchy parameter (see Subsection 2.1) to the instance g2z ∈ G such that nextg2z(h) ≡ h+ 2 (the simplest choice). Contexts. The explicit context of an MTT-judgement has the form: Γ ≡ x1 ∈ A1 Set, . . . , xn ∈ An Set where xi is a variable and Ai is an expression. We can map each declaration of Γ in a λ-item, so Γ itself becomes the λδ-context Cx ≡ λx1:A1 . . . λxn:An.Set. The implicit context of an MTT-judgement does not need an explicit mapping since we can exploit the implicit context of the corresponding λδ-judgement (at least as long as we are dealing just with the structural rules of MTT). Declarations: A Prop [Γ], A Set [Γ], a ∈ A Set [Γ], Γ Cont. A declaration judgement is mapped to a type assignment judgement (see Definition 10). Namely we map A Prop [Γ] to Cy.Cx ⊢g2z A : Prop, we map A Set [Γ] to Cy.Cx ⊢g2z A : Set and we map a ∈ A Set [Γ] to Cy.Cx ⊢g2z a : A in the implicit context Cy .Cx ⊢g2z A : Set. Here Cy .Cx refers to the concatenation of Cy and Cx. Notice that type assignment is invariant for conversion (modelling definitional equality) as stated by Figure 9(conv) and Theorem 4(6). Coming to the legal explicit context judgement Γ Cont, the experience of the author with λδ shows that such a judgement is useless (as it does not guarantee additional meta-theoretical properties) and heavy (as it introduces a mutual dependence between itself and A Set [Γ] at the meta-theory level). The point is that an unreferenced parameter does not need a legal declaration unless it is the formal argument of a function. So we propose not to map Γ Cont and to change the related rules (see Appendix A.3). Equalities: A1 = A2 Prop [Γ], A1 = A2 Set [Γ], a1 = a2 ∈ A Set [Γ]. An equality judgement is mapped to a contextual conversion judgement (see Definition 9). Namely, we map A1 = A2 S [Γ] to Cy.Cx ⊢ A1 ⇔ ∗ A2 in the implicit context Cy.Cx ⊢g2z A1 : S and Cy.Cx ⊢g2z A2 : S where S is either Prop or Set, and we map a1 = a2 ∈ A Set [Γ] to Cy.Cx ⊢ a1 ⇔ ∗ a2 in the implicit context Cy.Cx ⊢g2z a1 : A, Cy .Cx ⊢g2z a2 : A and Cy.Cx ⊢g2z A : Set. Notice that the conversion judgement is invariant for conversion itself (modelling definitional equality) being an equivalence relation. A.3 λδ Rules can express MTT Structural Rules Our proposal for the structural rules of MTT is shown in Figure 19. the prop-into-set rule can not be modelled, as it is, by λδ because λδ does not feature subtyping. Therefore our proposal is to make the coercion from Prop to Set explicit. Namely we declare a primitive constant pr of type λx:Prop.Set in the global context Cy and we set Figure 19(ps) modelled by Figure 9(appl). This solution is well known in the literature (see [Coquand and Huet 1988; van Benthem Jutting 1994a; de Bruijn 1994c]). The var rule. Our proposal for this rule is Figure 19(var) modelled by Figure 9(decl). Notice that the implicit context is respected because of Theorem 3(1). The seteq rule. This rule is Figure 19(seteq) modelled by Figure 9(conv) whose first premise is taken from the implicit context. ACM Transactions on Computational Logic, Vol. V, No. N, Month 20YY. λ-Types on the λ-Calculus with Abbreviations · 27 A Prop [Γ] pr(A) Set [Γ] ps A Set [Γ] x ∈ A Set [Γ, x ∈ A Set,∆] var a ∈ A1 Set [Γ] A1 = A2 Set [Γ] a ∈ A2 Set [Γ] seteq A Set [Γ] A = A Set [Γ] r A1 = A2 Set [Γ] A2 = A1 Set [Γ] s A1 = A Set [Γ] A = A2 Set [Γ] A1 = A2 Set [Γ] t A Prop [Γ] A = A Prop [Γ] r A1 = A2 Prop [Γ] A2 = A1 Prop [Γ] s A1 = A Prop [Γ] A = A2 Prop [Γ] A1 = A2 Prop [Γ] t a ∈ A Set [Γ] a = a ∈ A Set [Γ] r a1 = a2 ∈ A Set [Γ] a2 = a1 ∈ A Set [Γ] s a1 = a ∈ A Set [Γ] a = a2 ∈ A Set [Γ] a1 = a2 ∈ A Set [Γ] t A Set [Γ] B Set [Γ, x ∈ A Set] (x : A)B (x :A)Set [Γ] i A Set [Γ] B1 = B2 Set [Γ, x ∈ A Set] (x :A)B1 = (x :A)B2 (x :A)Set [Γ] i A Set [Γ] B Prop [Γ, x ∈ A Set] (x : A)B (x :A)Prop [Γ] i A Set [Γ] B1 = B2 Prop [Γ, x ∈ A Set] (x :A)B1 = (x :A)B2 (x :A)Prop [Γ] i A Set [Γ] b ∈ B Set [Γ, x ∈ A Set] (x :A)b ∈ (x : A)B (x :A)Set [Γ] i A Set [Γ] b1 = b2 ∈ B Set [Γ, x ∈ A Set] (x : A)b1 = (x :A)b2 ∈ (x :A)B (x :A)Set [Γ] i a ∈ A Set [Γ] B (x :A)Set [Γ] B(a) Set [Γ] e a ∈ A Set [Γ] B1 = B2 (x : A)Set [Γ] B1(a) = B2(a) Set [Γ] e a ∈ A Set [Γ] B (x :A)Prop [Γ] B(a) Prop [Γ] e a ∈ A Set [Γ] B1 = B2 (x : A)Prop [Γ] B1(a) = B2(a) Prop [Γ] e a ∈ A Set [Γ] b ∈ (x :A)B (x : A)Set [Γ] b(a) ∈ (x : A)B(a) Set [Γ] e a ∈ A Set [Γ] b1 = b2 ∈ (x :A)B (x : A)Set [Γ] b1(a) = b2(a) ∈ (x : A)B(a) Set [Γ] e Fig. 19. Our proposal for the structural rules of MTT The equivalence rules of the equality judgements are justified by the fact that context-dependent conversion is an equivalence relation. The complete list is in Figure 19 (labels: r, s, t). The derivable rules. Notice that [Nordström et al. 1990] suggests some additional structural rules (like a second seteq rule and some substitution rules) that are not included in MTT because they are derivable. In the λδ perspective we derive these rules from Theorem 1(4), Theorem 1(5), Theorem 3(4) and Theorem 13(1). The rules on classes. If we regard Prop and Set as primitive constants rather than judgement keywords, we can build expressions like (x1 : e1) . . . (xn : en)Set or (x1 : e1) . . . (xn : en)Prop (called types in MTT or categories in CTT [Martin-Löf 1984]). With these “classes” we can form the following judgements: B (x :A)Set [Γ] B1 = B2 (x : A)Set [Γ] B (x :A)Prop [Γ] B1 = B2 (x : A)Prop [Γ] b ∈ B (x :A)Set [Γ] b1 = b2 ∈ B (x : A)Set [Γ] (14) that we explain with the rules modelled by Figure 9(abst) and Theorem 1(6). These rules are shown in Figure 19 with the label: i. The elimination rules, modelled by Figure 9(appl) and Theorem 1(4), are shown in Figure 19 with the label: e. B. TOWARDS A DUALITY BETWEEN TERMS AND CONTEXTS The present appendix contains some hints on how the author plans to complete λδ by adding the items of the form ♮E both in terms and in contexts. In principle the ACM Transactions on Computational Logic, Vol. V, No. N, Month 20YY. 28 · Ferruccio Guidi need for these items was evident from the very start but they were not included in [Guidi 2006a] because of the technical problems they seemed to give. In particular the author did not see the importance of the iterated de Bruijn type assignment as a way to map T into C (Subsection 3.1) until the properties of λδ were made clear (especially Theorem 6(2), Theorem 6(1) and Theorem 9(3)). We would like to stress that the contents of this appendix are just a proposal for future research on λδ and have not been certified yet. In Appendix B.1 we introduce the ♮E items, In Appendix B.2 we propose the new term construction {E}.T as an application, in Appendix B.3 we propose to merge T and C in a single data type to avoid the replication of dual definitions and theorems in the perspective of certifying the properties of complete λδ. B.1 Complete λδ: Introducing the ♮E Items Looking at Definition 2 we see that the recursive constructions concern just the items of the form ♮V but the ♮E items (i.e. 〈E〉, (E), λy:E and δy←E) can be allowed as well. By so doing we obtain the following reformulation of T and C: Definition 23 complete syntax of terms and contexts. The complete sets of terms and contexts are defined as follows: T ≡ SortN | V | ♮T.T | ♮C.T (15) C ≡ SortN | W | ♮T.C | ♮C.C (16) where W is a set of names for variables and ♮T uses V while ♮C uses W. We call a recursive construction positive when its components belong to the same type and negative otherwise. This attribute is called the polarity of the construction. Notice that λμ̃ uses two different sets of variables as well. Once defined in this way, T and C are isomorphic through the polarity preserving transformations C : T → C and T :C → T defined below. Definition 24 the transformations C and T . The transformations C : T → C and T :C → T work as follows: (1 ) C(Sorth) = Sorth and T (Sorth) = Sorth. (2 ) C(x) = y and T (y) = x. (3 ) C(♮V.T ) = ♮C(V ).C(T ) and T (♮E.C) = ♮T (E).T (C). (4 ) C(♮C.T ) = ♮T (C).C(T ) and T (♮V.C) = ♮C(V ).T (C). Definition 23 opens some issues: we discuss the most relevant below. Focalized terms. When a term reference x points to a binder ♮V in a context C it may be the case that the rightmost item of C is not a sort. In that event we must consider its iterated de Bruijn type (see Theorem 6(2)). More precisely if C is X.y, where X is a part of a context, and if y points to ♮E, we consider D = X.E recursively (this is much like taking the iterated de Bruijn type of C except for the rightmost sort item that is irrelevant when searching for binders). This solution may look strange at a first glance but consider C = λy:E.y: this is the empty context whose “hole” is y in the sense of [Curien and Herbelin 2000]. Normally references to the empty context are not legal but in our case the “hole” ACM Transactions on Computational Logic, Vol. V, No. N, Month 20YY. λ-Types on the λ-Calculus with Abbreviations · 29 is typed explicitly so we can foresee its contents by inspecting its type. This means that for E = λx:V.Sortnextg(n) the focalized term (λy:E.y, x) is legal and the term reference x points to λx:V . Furthermore that reference continues to point to the same binder when C is instantiated and reduced as the the examples show. (1) Legal instantiation with F = λx:V.Sortn: ((F ).λy:E.y, x). (2) β-contraction: (δy←F.y, x). (3) δ-expansion: (δy←F.F , x). (4) ζ-contraction: (F, x). As we see, everything works fine because the item λx:V must appear in F as well as in E in order for the instantiation to be legal (i.e. well typed). Pushing. When moving an term item ♮V into a context, as we might need to do when the term and the context themselves are the components of a focalized term, we need to preserve the binders pointed by the references. So, when the context has the form X.y where y points to ♮E, we must move ♮V into E recursively. In the case of the abstraction, this amounts to updating the explicit type of the context “hole” in a way that makes it possible to fill the “hole” with the term item itself through a legal instantiation. Reduction. The β-redexes are (W ).λx:V (from Subsection 2.4) and symmetrically (F ).λy:E. The abbreviations δx←V.C do not ζ-reduce (from [Guidi 2006b]) and symmetrically the abbreviations δy←E.T do not ζ-reduce either. B.2 Contexts as Aggregates We said that the k-uple (Vk−1, . . . , V0) at position (h, 0) in the type hierarchy is denoted by the context F = δxk−1←Vk−1 . . . δx0←V0.Sorth More generally the binders ♮V of a context E (as well as the binders ♮E of a term V ) can be seen as the fields of an aggregate structure. These fields can be definitions (denoted by the δx←V items) or declarations (denoted by the λx:V items) and can be dependent. In order to be effective, aggregates need a projection mechanism that allows to reed their fields. To this aim we propose the item {E} that belongs to the ♮E item scheme and the term construction {E}.T that we call projection. The basic idea is that {F}.xi must reduce to Vi, so we set the following sequential reduction rule: if E ⊢ T1 → ∗ T2 and if T2 does not refer to E then {E}.T1 →π T2. Notice that {E}.T might be related to the with instruction of the pascal programming language [Jensen and Wirth 1981] and might look like: with E do T . Following the “contexts as aggregates” interpretation, we might expect to type F with F1 = λxk−1:Wk−1 . . . λx0:W0.Sortnextg(h) where each Wi is the type of Vi. Nevertheless the type of F is F2 = δxk−1←Vk−1 . . . δx0←V0.Sortnextg(h) according to Feature 1 but notice that F1 ≤g F2 (this is the partial order of Subsection 3.5). This consideration shows that it could make sense to investigate the extension of λδ with a subtyping relation based on ≤g. B.3 Unified λδ: Introducing Polarized Terms In this subsection we propose the notion of a polarized term: an expression capable of representing both a term and a context (in the sense of Definition 2) in a way that turns the transformations C and T into the identity functions. ACM Transactions on Computational Logic, Vol. V, No. N, Month 20YY. 30 · Ferruccio Guidi polarity(P, P ) = ⊤ refl polarity(b♮Q.P , P ) = ⊤ fst polarity(b♮Q.P ,Q) = b snd polarity(P1, P ) = b1 polarity(P,P2) = b2 polarity(P1, P2) = b1 ↔ b2 trans Fig. 20. Relative polarity assignment rules The basic idea consists in decorating the recursive term constructions with the information on their polarity represented as a boolean value. Let us denote the data type of the boolean values with B ≡ {⊥,⊤} and let us assume that ⊤ represents a positive polarity, then a polarized term is as follows. Definition 25 syntax of polarized terms. The set of polarized terms is defined as follows: P ≡ SortN | V | BλV:P.P | BδV←P.P | B(P).P | B〈P〉.P (17) Definition 25 opens the issue of deciding whether a Q ∈ P can be mapped back to a V ∈ T or to a E ∈ C. Clearly the fact that the transformations C and T are mapped to the identity functions on P says that this information, which we call the absolute polarity of Q, is not recoverable. What we can recover is the relative polarity of Q with respect to a superterm P of Q This is to say that we can know if P and Q represent two elements of the same type or not. Definition 26 relative polarity assignment. The partial function polarity(P,Q), that returns ⊤ if the terms P and Q have the same absolute polarity, is defined by the rules shown in Figure 20 where ↔ denotes the boolean coimplication (i.e. the negated xor operation). We conjecture that the knowledge of relative polarity is enough to treat the version of λδ based on polarized terms. We call this calculus unified λδ or 1λδ. As an example let us consider the restrictions on reduction mentioned in Appendix B.1. The unified β-redex takes the form b(Q1).bλz:Q2, while ζ-reduction is allowed on the items ⊤δz←Q and not allowed on the items ⊥δz←Q. C. A NOTE ON THE CURRENT STATE OF THE FORMAL SPECIFICATION In this appendix we discuss the current state of the definitions that formally specify λδχ in the the Calculus of Inductive Constructions [Guidi 2006a] in terms of modifications with respect to their initial state [Guidi 2006b]. Firstly we set up a mechanism to avoid the need of exchanging the context binders in the proof of Theorem 11(7). In particular we defined an extension of the lift function and an extension of the drop function [Guidi 2006b] that apply a finite number of relocations to a term. The “relocation parameters” (i.e. the arguments h and i of the lift function) are contained in a list of pairs (h, i). Here s will always denote a variable for such a list. These definitions are given in Definition 27 and Definition 28 below. Definition 27 the multiple relocation function.

برای دانلود متن کامل این مقاله و بیش از 32 میلیون مقاله دیگر ابتدا ثبت نام کنید

ثبت نام

اگر عضو سایت هستید لطفا وارد حساب کاربری خود شوید

منابع مشابه

λ-Types on the λ-Calculus with Abbreviations: a Certified Specification

In this paper the author presents λδ, a λ-typed λ-calculus with a single λ binder and abbreviations. The formal properties of λδ, that include the standard requirements for a typed λ-calculus, have been certified by the author with the proof assistant COQ. The presentation focuses on motivating the calculus and the corpus of definitions on which its specification in COQ is based.

متن کامل

The Formal System λδ

The formal system λδ is a typed λ-calculus that pursues the unification of terms, types, environments and contexts as the main goal. λδ takes some features from the Automath-related λ-calculi and some from the pure type systems, but differs from both in that it does not include the Π construction while it provides for an abbreviation mechanism at the level of terms. λδ enjoys some important des...

متن کامل

Extensional Universal Types for Call-by-Value

Overview We give: 1. the λ c 2 η-calculus (and λ c 2-calculus): a second-order polymorphic call-by-value calculus with extensional universal types 2. • λ c 2 η-models: categorical semantics for λ c 2 η-calculus • monadic λ c 2 η-models: categorical semantics for λ c 2 η-calculus with the focus on monadic metalanguages like Haskell 3. relevant parametric models: domain theoretic concrete models ...

متن کامل

Rewriting Modulo \beta in the \lambda\Pi-Calculus Modulo

The λ Π-calculus Modulo is a variant of the λ -calculus with dependent types where β -conversion is extended with user-defined rewrite rules. It is an expressive logical framework and has been used to encode logics and type systems in a shallow way. Basic properties such as subject reduction or uniqueness of types do not hold in general in the λ Π-calculus Modulo. However, they hold if the rewr...

متن کامل

Urzyczyn and Loader are Logically Related

In simply typed λ-calculus with one ground type the following theorem due to Loader holds. (i) Given the full model F over a finite set, the question whether some element f ∈ F is λ-definable is undecidable. In the λ-calculus with intersection types based on countably many atoms, the following is proved by Urzyczyn. (ii) It is undecidable whether a type is inhabited. Both statements are major r...

متن کامل

Short Proofs of Strong Normalization

This paper presents simple, syntactic strong normalization proofs for the simply-typed λ-calculus and the polymorphic λ-calculus (system F) with the full set of logical connectives, and all the permutative reductions. The normalization proofs use translations of terms and types of λ→,∧,∨,⊥ to terms and types of λ→ and from F∀,∃,→,∧,∨,⊥ to F∀,→.

متن کامل

ذخیره در منابع من


  با ذخیره ی این منبع در منابع من، دسترسی به آن را برای استفاده های بعدی آسان تر کنید

برای دانلود متن کامل این مقاله و بیش از 32 میلیون مقاله دیگر ابتدا ثبت نام کنید

ثبت نام

اگر عضو سایت هستید لطفا وارد حساب کاربری خود شوید

عنوان ژورنال:

دوره   شماره 

صفحات  -

تاریخ انتشار 2006